home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / PROGRAMM / PASCAL / 0188.ZIP / ASYNC.INC < prev    next >
Text File  |  1986-01-25  |  16KB  |  402 lines

  1. === Qmodem Capture File ===
  2. Enter choice: 4
  3. Capture Buffer Transfer
  4. No error detection/correction
  5.  
  6. Opening capture buffer...
  7. {----------------------------------------------------------------------}
  8. {                                                                      } 
  9. {                          ASYNC.INC                                   } 
  10. {                                                                      } 
  11. {  Async Communication Routines                                        } 
  12. {  by Michael Quinlan                                                  } 
  13. {  with a bug fixed by Scott Herr                                      }
  14. {  made PCjr-compatible by W. M. Miller                                }
  15. {  Highly dependant on the IBM PC and PC DOS 2.0                       } 
  16. {                                                                      } 
  17. {  based on the DUMBTERM program by CJ Dunford in the January 1984     } 
  18. {  issue of PC Tech Journal.                                           } 
  19. {                                                                      } 
  20. {  Entry points:                                                       } 
  21. {                                                                      } 
  22. {    Async_Init                                                        } 
  23. {      Performs initialization.                                        }
  24. {                                                                      } 
  25. {    Async_Open(Port, Baud : Integer;                                  } 
  26. {               Parity : Char;                                         } 
  27. {               WordSize, StpBits : Integer) : Boolean                 } 
  28. {      Sets up interrupt vector, initialies the COM port for           } 
  29. {      processing, sets pointers to the buffer.  Returns FALSE if COM  } 
  30. {      port not installed.                                             } 
  31. {                                                                      }
  32. {    Async_Buffer_Check(var C : Char) : Boolean                        }
  33. {      If a character is available, returns TRUE and moves the         }
  34. {        character from the buffer to the parameter                    }
  35. {      Otherwise, returns FALSE                                        }
  36. {                                                                      }
  37. {    Async_Send(C : Char)                                              }
  38. {      Transmits the character.                                        }
  39. {                                                                      }
  40. {    Async_Send_String(S : LStr)                                       }
  41. {      Calls Async_Send to send each character of S.                   }
  42. {                                                                      }
  43. {    Async_Close                                                       }
  44. {      Turn off the COM port interrupts.                               }
  45. {      **MUST** BE CALLED BEFORE EXITING YOUR PROGRAM; otherwise you   }
  46. {      will see some really strange errors and have to re-boot.        }
  47. {                                                                      }
  48. {----------------------------------------------------------------------}
  49.  
  50. { global declarations }
  51.  
  52. type
  53.   LStr = String[255];  { generic string type for parameters }
  54.  
  55. const
  56.   UART_THR = $00;    { offset from base of UART Registers for IBM PC } 
  57.   UART_RBR = $00; 
  58.   UART_IER = $01; 
  59.   UART_IIR = $02; 
  60.   UART_LCR = $03; 
  61.   UART_MCR = $04; 
  62.   UART_LSR = $05; 
  63.   UART_MSR = $06; 
  64.  
  65.   I8088_IMR = $21;   { port address of the Interrupt Mask Register } 
  66.  
  67. const 
  68.   Async_DSeg_Save : Integer = 0;  { Save DS reg in Code Segment for interrupt 
  69.                                     routine } 
  70.  
  71. const
  72.   Async_Buffer_Max = 4095;
  73.  
  74. var 
  75.   Async_Buffer       : Array[0..Async_Buffer_Max] of char; 
  76.  
  77.   Async_Open_Flag    : Boolean;   { true if Open but no Close } 
  78.   Async_Port         : Integer;   { current Open port number (1 or 2) } 
  79.   Async_Base         : Integer;   { base for current open port } 
  80.   Async_Irq          : Integer;   { irq for current open port } 
  81.  
  82.   Async_Buffer_Overflow : Boolean;  { True if buffer overflow has happened } 
  83.   Async_Buffer_Used     : Integer; 
  84.   Async_MaxBufferUsed   : Integer; 
  85.  
  86.     { Async_Buffer is empty if Head = Tail } 
  87.   Async_Buffer_Head  : Integer;   { Locn in Async_Buffer to put next char } 
  88.   Async_Buffer_Tail  : Integer;   { Locn in Async_Buffer to get next char } 
  89.   Async_Buffer_NewTail : Integer;
  90.  
  91.   Async_BIOS_Port_Table : Array[1..2] of Integer absolute $40:0;
  92.                { This table is initialized by BIOS equipment determination
  93.                  code at boot time to contain the base addresses for the
  94.                  installed async adapters.  A value of 0 means "not in-
  95.                  stalled." }
  96.  
  97. const 
  98.   Async_Num_Bauds = 8; 
  99.   Async_Baud_Table : array [1..Async_Num_Bauds] of record 
  100.                                                      Baud, Bits : integer
  101.                                                    end
  102.                    = ((Baud:110;  Bits:$00), 
  103.                       (Baud:150;  Bits:$20), 
  104.                       (Baud:300;  Bits:$40), 
  105.                       (Baud:600;  Bits:$60), 
  106.                       (Baud:1200; Bits:$80), 
  107.                       (Baud:2400; Bits:$A0), 
  108.                       (Baud:4800; Bits:$C0), 
  109.                       (Baud:9600; Bits:$E0)); 
  110.  
  111.  
  112. procedure BIOS_RS232_Init(ComPort, ComParm : Integer); 
  113. { Issue Interrupt $14 to initialize the UART } 
  114. { See the IBM PC Technical Reference Manual for the format of ComParm } 
  115. var 
  116.   Regs : record 
  117.            ax, bx, cx, dx, bp, si, di, ds, es, flag : Integer 
  118.          end; 
  119. begin 
  120.   with Regs do 
  121.     begin 
  122.       ax := ComParm and $00FF;  { AH=0; AL=ComParm } 
  123.       dx := ComPort;
  124.       Intr($14, Regs)
  125.     end 
  126. end; { BIOS_RS232_Init } 
  127.  
  128. procedure DOS_Set_Intrpt(v, s, o : integer); 
  129. { call DOS to set an interrupt vector } 
  130. var 
  131.   Regs : Record 
  132.            ax, bx, cx, dx, bp, si, di, ds, es, flag : integer 
  133.          end; 
  134. begin 
  135.   with Regs do 
  136.     begin 
  137.       ax := $2500 + (v and $00FF); 
  138.       ds := s; 
  139.       dx := o; 
  140.       MsDos(Regs) 
  141.     end 
  142. end; { DOS_Set_Intrpt } 
  143.  
  144. {----------------------------------------------------------------------} 
  145. {                                                                      } 
  146. {  ASYNCISR.INC - Interrupt Service Routine                            }
  147. {                                                                      }
  148. {----------------------------------------------------------------------} 
  149.  
  150. procedure Async_Isr; 
  151. { Interrupt Service Routine } 
  152. { Invoked when the UART has received a byte of data from the 
  153.   communication line } 
  154.  
  155. { re-written 9/10/84 to be entirely in machine language; original source 
  156.   left as comments } 
  157.  
  158. begin 
  159.  
  160.   {NOTE: on entry, Turbo Pascal has already PUSHed BP and SP } 
  161.  
  162.   Inline( 
  163.       { save all registers used } 
  164.     $50/                           { PUSH AX } 
  165.     $53/                           { PUSH BX } 
  166.     $52/                           { PUSH DX } 
  167.     $1E/                           { PUSH DS } 
  168.     $FB/                           { STI } 
  169.       { set up the DS register to point to Turbo Pascal's data segment }
  170.     $2E/$FF/$36/Async_Dseg_Save/   { PUSH CS:Async_Dseg_Save }
  171.     $1F/                           { POP DS } 
  172.       { get the incomming character } 
  173.       { Async_Buffer[Async_Buffer_Head] := Chr(Port[UART_RBR + Async_Base]); } 
  174.     $8B/$16/Async_Base/            { MOV DX,Async_Base } 
  175.     $EC/                           { IN AL,DX } 
  176.     $8B/$1E/Async_Buffer_Head/     { MOV BX,Async_Buffer_Head } 
  177.     $88/$87/Async_Buffer/          { MOV Async_Buffer[BX],AL } 
  178.       { Async_Buffer_NewHead := Async_Buffer_Head + 1; } 
  179.     $43/                           { INC BX } 
  180.       { if Async_Buffer_NewHead > Async_Buffer_Max then 
  181.           Async_Buffer_NewHead := 0; } 
  182.     $81/$FB/Async_Buffer_Max/      { CMP BX,Async_Buffer_Max } 
  183.     $7E/$02/                       { JLE L001 } 
  184.     $33/$DB/                       { XOR BX,BX } 
  185.       { if Async_Buffer_NewHead = Async_Buffer_Tail then 
  186.           Async_Buffer_Overflow := TRUE 
  187.         else } 
  188. {L001:} 
  189.     $3B/$1E/Async_Buffer_Tail/     { CMP BX,Async_Buffer_Tail } 
  190.     $75/$08/                       { JNE L002 } 
  191.     $C6/$06/Async_Buffer_Overflow/$01/ { MOV Async_Buffer_Overflow,1 } 
  192.     $90/                           { NOP generated by assembler for some reason 
  193.  
  194.     $EB/$16/                       { JMP SHORT L003 }
  195.       { begin 
  196.           Async_Buffer_Head := Async_Buffer_NewHead; 
  197.           Async_Buffer_Used := Async_Buffer_Used + 1; 
  198.           if Async_Buffer_Used > Async_MaxBufferUsed then 
  199.             Async_MaxBufferUsed := Async_Buffer_Used 
  200.         end; } 
  201. {L002:} 
  202.     $89/$1E/Async_Buffer_Head/     { MOV Async_Buffer_Head,BX } 
  203.     $FF/$06/Async_Buffer_Used/     { INC Async_Buffer_Used } 
  204.     $8B/$1E/Async_Buffer_Used/     { MOV BX,Async_Buffer_Used } 
  205.     $3B/$1E/Async_MaxBufferUsed/   { CMP BX,Async_MaxBufferUsed } 
  206.     $7E/$04/                       { JLE L003 } 
  207.     $89/$1E/Async_MaxBufferUsed/   { MOV Async_MaxBufferUsed,BX } 
  208. {L003:} 
  209.       { disable interrupts } 
  210.     $FA/                           { CLI } 
  211.       { Port[$20] := $20; }  { use non-specific EOI } 
  212.     $B0/$20/                       { MOV AL,20h } 
  213.     $E6/$20/                       { OUT 20h,AL } 
  214.       { restore the registers then use IRET to return } 
  215.       { the last two POPs are required because Turbo Pascal PUSHes these regs 
  216.         before we get control.  The manual doesn't so it, but that is what
  217.         really happens }
  218.     $1F/                           { POP DS } 
  219.     $5A/                           { POP DX } 
  220.     $5B/                           { POP BX } 
  221.     $58/                           { POP AX } 
  222.     $5C/                           { POP SP } 
  223.     $5D/                           { POP BP } 
  224.     $CF)                           { IRET } 
  225. end; { Async_Isr } 
  226.  
  227. procedure Async_Init; 
  228. { initialize variables } 
  229. begin 
  230.   Async_DSeg_Save := DSeg; 
  231.   Async_Open_Flag := FALSE; 
  232.   Async_Buffer_Overflow := FALSE; 
  233.   Async_Buffer_Used := 0; 
  234.   Async_MaxBufferUsed := 0; 
  235. end; { Async_Init } 
  236.  
  237. procedure Async_Close; 
  238. { reset the interrupt system when UART interrupts no longer needed } 
  239. var
  240.   i, m : Integer;
  241. begin 
  242.   if Async_Open_Flag then 
  243.     begin 
  244.  
  245.       { disable the IRQ on the 8259 } 
  246.       Inline($FA);         { disable interrupts } 
  247.       i := Port[I8088_IMR];        { get the interrupt mask register } 
  248.       m := 1 shl Async_Irq;        { set mask to turn off interrupt } 
  249.       Port[I8088_IMR] := i or m; 
  250.  
  251.       { disable the 8250 data ready interrupt } 
  252.       Port[UART_IER + Async_Base] := 0; 
  253.  
  254.       { disable OUT2 on the 8250 } 
  255.       Port[UART_MCR + Async_Base] := 0; 
  256.       Inline($FB);          { enable interrupts }
  257.  
  258.       { re-initialize our data areas so we know the port is closed } 
  259.       Async_Open_Flag := FALSE 
  260.  
  261.     end 
  262. end; { Async_Close }
  263.  
  264. function Async_Open(ComPort       : Integer; 
  265.                     BaudRate      : Integer; 
  266.                     Parity        : Char; 
  267.                     WordSize      : Integer; 
  268.                     StopBits      : Integer) : Boolean; 
  269. { open a communications port } 
  270. var 
  271.   ComParm : Integer; 
  272.   i, m : Integer; 
  273. begin 
  274.   if Async_Open_Flag then Async_Close; 
  275.  
  276.   if (ComPort = 2) and (Async_BIOS_Port_Table[2] <> 0) then
  277.     Async_Port := 2
  278.   else
  279.     Async_Port := 1;  { default to COM1 }
  280.   Async_Base := Async_BIOS_Port_Table[Async_Port];
  281.   Async_Irq := Hi(Async_Base) + 1;
  282.  
  283.   if (Port[UART_IIR + Async_Base] and $00F8) <> 0 then 
  284.     Async_Open := FALSE 
  285.   else
  286.     begin 
  287.       Async_Buffer_Head := 0; 
  288.       Async_Buffer_Tail := 0; 
  289.       Async_Buffer_Overflow := FALSE; 
  290.  
  291.   { Build the ComParm for RS232_Init } 
  292.   { See Technical Reference Manual for description } 
  293.  
  294.       ComParm := $0000; 
  295.  
  296.   { Set up the bits for the baud rate } 
  297.       i := 0; 
  298.       repeat 
  299.         i := i + 1 
  300.       until (Async_Baud_Table[i].Baud = BaudRate) or (i = Async_Num_Bauds); 
  301.       ComParm := ComParm or Async_Baud_Table[i].Bits; 
  302.  
  303.       if Parity in ['E', 'e'] then ComParm := ComParm or $0018
  304.       else if Parity in ['O', 'o'] then ComParm := ComParm or $0008 
  305.       else ComParm := ComParm or $0000;  { default to No parity } 
  306.  
  307.       if WordSize = 7 then ComParm := ComParm or $0002 
  308.       else ComParm := ComParm or $0003;  { default to 8 data bits }
  309.  
  310.       if StopBits = 2 then ComParm := ComParm or $0004 
  311.       else ComParm := ComParm or $0000;  { default to 1 stop bit } 
  312.  
  313.   { use the BIOS COM port initialization routine to save typing the code } 
  314.       BIOS_RS232_Init(Async_Port - 1, ComParm); 
  315.  
  316.       DOS_Set_Intrpt(Async_Irq + 8, CSeg, Ofs(Async_Isr)); 
  317.  
  318.   { read the RBR and reset any possible pending error conditions } 
  319.   { first turn off the Divisor Access Latch Bit to allow access to RBR, etc. } 
  320.  
  321.       Inline($FA);  { disable interrupts } 
  322.  
  323.       Port[UART_LCR + Async_Base] := Port[UART_LCR + Async_Base] and $7F; 
  324.   { read the Line Status Register to reset any errors it indicates } 
  325.       i := Port[UART_LSR + Async_Base];
  326.   { read the Receiver Buffer Register in case it contains a character }
  327.       i := Port[UART_RBR + Async_Base]; 
  328.  
  329.   { enable the irq on the 8259 controller } 
  330.       i := Port[I8088_IMR];  { get the interrupt mask register } 
  331.       m := (1 shl Async_Irq) xor $00FF;
  332.       Port[I8088_IMR] := i and m; 
  333.  
  334.   { enable the data ready interrupt on the 8250 } 
  335.       Port[UART_IER + Async_Base] := $01; { enable data ready interrupt } 
  336.  
  337.   { enable OUT2 on 8250 } 
  338.       i := Port[UART_MCR + Async_Base]; 
  339.       Port[UART_MCR + Async_Base] := i or $08; 
  340.  
  341.       Inline($FB); { enable interrupts }
  342.       Async_Open_Flag := TRUE;  { bug fix by Scott Herr }
  343.       Async_Open := TRUE 
  344.     end 
  345. end; { Async_Open } 
  346.  
  347. function Async_Buffer_Check(var C : Char) : Boolean; 
  348. { see if a character has been received; return it if yes }
  349. begin
  350.   if Async_Buffer_Head = Async_Buffer_Tail then 
  351.     Async_Buffer_Check := FALSE 
  352.   else 
  353.     begin 
  354.       C := Async_Buffer[Async_Buffer_Tail];
  355.       Async_Buffer_Tail := Async_Buffer_Tail + 1; 
  356.       if Async_Buffer_Tail > Async_Buffer_Max then 
  357.         Async_Buffer_Tail := 0; 
  358.       Async_Buffer_Used := Async_Buffer_Used - 1; 
  359.       Async_Buffer_Check := TRUE 
  360.     end 
  361. end; { Async_Buffer_Check } 
  362.  
  363. procedure Async_Send(C : Char); 
  364. { transmit a character } 
  365. var 
  366.   i, m, counter : Integer; 
  367. begin 
  368.   Port[UART_MCR + Async_Base] := $0B; { turn on OUT2, DTR, and RTS } 
  369.  
  370.   { wait for CTS } 
  371.   counter := MaxInt;
  372.   while (counter <> 0) and ((Port[UART_MSR + Async_Base] and $10) = 0) do
  373.     counter := counter - 1; 
  374.  
  375.   { wait for Transmit Hold Register Empty (THRE) } 
  376.   if counter <> 0 then counter := MaxInt;
  377.   while (counter <> 0) and ((Port[UART_LSR + Async_Base] and $20) = 0) do
  378.     counter := counter - 1; 
  379.  
  380.   if counter <> 0 then 
  381.     begin 
  382.       { send the character } 
  383.       Inline($FA); { disable interrupts } 
  384.       Port[UART_THR + Async_Base] := Ord(C); 
  385.       Inline($FB) { enable interrupts } 
  386.     end 
  387.   else 
  388.     writeln('<<<TIMEOUT>>>'); 
  389.  
  390. end; { Async_Send } 
  391.  
  392. procedure Async_Send_String(S : LStr); 
  393. { transmit a string } 
  394. var
  395.   i : Integer;
  396. begin 
  397.   for i := 1 to length(S) do
  398.     Async_Send(S[i])
  399. end; { Async_Send_String }
  400. Capture buffer closed.
  401.  
  402.